home *** CD-ROM | disk | FTP | other *** search
-
-
-
- CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS)))) CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS))))
-
-
-
- NNNNAAAAMMMMEEEE
- CLATBS - solve one of the triangular systems A * x = s*b, A**T * x =
- s*b, or A**H * x = s*b,
-
- SSSSYYYYNNNNOOOOPPPPSSSSIIIISSSS
- SUBROUTINE CLATBS( UPLO, TRANS, DIAG, NORMIN, N, KD, AB, LDAB, X, SCALE,
- CNORM, INFO )
-
- CHARACTER DIAG, NORMIN, TRANS, UPLO
-
- INTEGER INFO, KD, LDAB, N
-
- REAL SCALE
-
- REAL CNORM( * )
-
- COMPLEX AB( LDAB, * ), X( * )
-
- IIIIMMMMPPPPLLLLEEEEMMMMEEEENNNNTTTTAAAATTTTIIIIOOOONNNN
- These routines are part of the SCSL Scientific Library and can be loaded
- using either the -lscs or the -lscs_mp option. The -lscs_mp option
- directs the linker to use the multi-processor version of the library.
-
- When linking to SCSL with -lscs or -lscs_mp, the default integer size is
- 4 bytes (32 bits). Another version of SCSL is available in which integers
- are 8 bytes (64 bits). This version allows the user access to larger
- memory sizes and helps when porting legacy Cray codes. It can be loaded
- by using the -lscs_i8 option or the -lscs_i8_mp option. A program may use
- only one of the two versions; 4-byte integer and 8-byte integer library
- calls cannot be mixed.
-
- PPPPUUUURRRRPPPPOOOOSSSSEEEE
- CLATBS solves one of the triangular systems A * x = s*b, A**T * x = s*b,
- or A**H * x = s*b, with scaling to prevent overflow, where A is an upper
- or lower triangular band matrix. Here A' denotes the transpose of A, x
- and b are n-element vectors, and s is a scaling factor, usually less than
- or equal to 1, chosen so that the components of x will be less than the
- overflow threshold. If the unscaled problem will not cause overflow, the
- Level 2 BLAS routine CTBSV is called. If the matrix A is singular
- (A(j,j) = 0 for some j), then s is set to 0 and a non-trivial solution to
- A*x = 0 is returned.
-
-
- AAAARRRRGGGGUUUUMMMMEEEENNNNTTTTSSSS
- UPLO (input) CHARACTER*1
- Specifies whether the matrix A is upper or lower triangular. =
- 'U': Upper triangular
- = 'L': Lower triangular
-
- TRANS (input) CHARACTER*1
- Specifies the operation applied to A. = 'N': Solve A * x = s*b
- (No transpose)
-
-
-
- PPPPaaaaggggeeee 1111
-
-
-
-
-
-
- CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS)))) CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS))))
-
-
-
- = 'T': Solve A**T * x = s*b (Transpose)
- = 'C': Solve A**H * x = s*b (Conjugate transpose)
-
- DIAG (input) CHARACTER*1
- Specifies whether or not the matrix A is unit triangular. = 'N':
- Non-unit triangular
- = 'U': Unit triangular
-
- NORMIN (input) CHARACTER*1
- Specifies whether CNORM has been set or not. = 'Y': CNORM
- contains the column norms on entry
- = 'N': CNORM is not set on entry. On exit, the norms will be
- computed and stored in CNORM.
-
- N (input) INTEGER
- The order of the matrix A. N >= 0.
-
- KD (input) INTEGER
- The number of subdiagonals or superdiagonals in the triangular
- matrix A. KD >= 0.
-
- AB (input) COMPLEX array, dimension (LDAB,N)
- The upper or lower triangular band matrix A, stored in the first
- KD+1 rows of the array. The j-th column of A is stored in the j-
- th column of the array AB as follows: if UPLO = 'U', AB(kd+1+i-
- j,j) = A(i,j) for max(1,j-kd)<=i<=j; if UPLO = 'L', AB(1+i-j,j)
- = A(i,j) for j<=i<=min(n,j+kd).
-
- LDAB (input) INTEGER
- The leading dimension of the array AB. LDAB >= KD+1.
-
- X (input/output) COMPLEX array, dimension (N)
- On entry, the right hand side b of the triangular system. On
- exit, X is overwritten by the solution vector x.
-
- SCALE (output) REAL
- The scaling factor s for the triangular system A * x = s*b, A**T
- * x = s*b, or A**H * x = s*b. If SCALE = 0, the matrix A is
- singular or badly scaled, and the vector x is an exact or
- approximate solution to A*x = 0.
-
- CNORM (input or output) REAL array, dimension (N)
-
- If NORMIN = 'Y', CNORM is an input argument and CNORM(j) contains
- the norm of the off-diagonal part of the j-th column of A. If
- TRANS = 'N', CNORM(j) must be greater than or equal to the
- infinity-norm, and if TRANS = 'T' or 'C', CNORM(j) must be
- greater than or equal to the 1-norm.
-
- If NORMIN = 'N', CNORM is an output argument and CNORM(j) returns
- the 1-norm of the offdiagonal part of the j-th column of A.
-
-
-
-
- PPPPaaaaggggeeee 2222
-
-
-
-
-
-
- CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS)))) CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS))))
-
-
-
- INFO (output) INTEGER
- = 0: successful exit
- < 0: if INFO = -k, the k-th argument had an illegal value
-
- FFFFUUUURRRRTTTTHHHHEEEERRRR DDDDEEEETTTTAAAAIIIILLLLSSSS
- A rough bound on x is computed; if that is less than overflow, CTBSV is
- called, otherwise, specific code is used which checks for possible
- overflow or divide-by-zero at every operation.
-
- A columnwise scheme is used for solving A*x = b. The basic algorithm if
- A is lower triangular is
-
- x[1:n] := b[1:n]
- for j = 1, ..., n
- x(j) := x(j) / A(j,j)
- x[j+1:n] := x[j+1:n] - x(j) * A[j+1:n,j]
- end
-
- Define bounds on the components of x after j iterations of the loop:
- M(j) = bound on x[1:j]
- G(j) = bound on x[j+1:n]
- Initially, let M(0) = 0 and G(0) = max{x(i), i=1,...,n}.
-
- Then for iteration j+1 we have
- M(j+1) <= G(j) / | A(j+1,j+1) |
- G(j+1) <= G(j) + M(j+1) * | A[j+2:n,j+1] |
- <= G(j) ( 1 + CNORM(j+1) / | A(j+1,j+1) | )
-
- where CNORM(j+1) is greater than or equal to the infinity-norm of column
- j+1 of A, not counting the diagonal. Hence
-
- G(j) <= G(0) product ( 1 + CNORM(i) / | A(i,i) | )
- 1<=i<=j
- and
-
- |x(j)| <= ( G(0) / |A(j,j)| ) product ( 1 + CNORM(i) / |A(i,i)| )
- 1<=i< j
-
- Since |x(j)| <= M(j), we use the Level 2 BLAS routine CTBSV if the
- reciprocal of the largest M(j), j=1,..,n, is larger than
- max(underflow, 1/overflow).
-
- The bound on x(j) is also used to determine when a step in the columnwise
- method can be performed without fear of overflow. If the computed bound
- is greater than a large constant, x is scaled to prevent overflow, but if
- the bound overflows, x is set to 0, x(j) to 1, and scale to 0, and a
- non-trivial solution to A*x = 0 is found.
-
- Similarly, a row-wise scheme is used to solve A**T *x = b or A**H *x =
- b. The basic algorithm for A upper triangular is
-
- for j = 1, ..., n
-
-
-
- PPPPaaaaggggeeee 3333
-
-
-
-
-
-
- CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS)))) CCCCLLLLAAAATTTTBBBBSSSS((((3333SSSS))))
-
-
-
- x(j) := ( b(j) - A[1:j-1,j]' * x[1:j-1] ) / A(j,j)
- end
-
- We simultaneously compute two bounds
- G(j) = bound on ( b(i) - A[1:i-1,i]' * x[1:i-1] ), 1<=i<=j
- M(j) = bound on x(i), 1<=i<=j
-
- The initial values are G(0) = 0, M(0) = max{b(i), i=1,..,n}, and we add
- the constraint G(j) >= G(j-1) and M(j) >= M(j-1) for j >= 1. Then the
- bound on x(j) is
-
- M(j) <= M(j-1) * ( 1 + CNORM(j) ) / | A(j,j) |
-
- <= M(0) * product ( ( 1 + CNORM(i) ) / |A(i,i)| )
- 1<=i<=j
-
- and we can safely call CTBSV if 1/M(n) and 1/G(n) are both greater than
- max(underflow, 1/overflow).
-
-
- SSSSEEEEEEEE AAAALLLLSSSSOOOO
- INTRO_LAPACK(3S), INTRO_SCSL(3S)
-
- This man page is available only online.
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- PPPPaaaaggggeeee 4444
-
-
-
-